home *** CD-ROM | disk | FTP | other *** search
- .XLIST
- PAGE 60,132
- TITLE UNDERLI2.ASM - Alters BIOS registers to enable underlining
- SUBTTL Opening Comments
- .LIST
- ;-----------------------------------------------------------------------------
- ; SUMMARY
- ;-----------------------------------------------------------------------------
-
- ; Turn EGA underlining on or off. Also change specified
- ; palette values for a mode command.
- ;
- ; Usage
- ; underli2 [on|off|switch|keep|unload|#] [ /s] [/p<k1>=<n1>]
- ; [/p<k2>=<n2>] ...
- ; where
- ; "on" turns underlining on.
- ; "off" turns underline off.
- ; "switch" reverses the underlining setting.
- ; "keep" keeps the underlining setting.
- ; "unload" removes underli2 from memory.
- ; # turns on underlining at scan line #.
- ; If you don't specify one of these values,
- ; underli2 reverses the underlining setting.
- ; "/s" resets all unspecified palettes to their
- ; standard values.
- ; "/p<ki>=<ni>" sets palette ki (maximum 15)
- ; to value ni (maximum 63 = 03FH). Enter ki and ni
- ; as decimal numbers.
- ; Upper and lower case are both OK. You can use "-" in place of "/".
- ; The = separator between <ki> and <ni> can be any non-numeric
- ; character. You can use any sequence of command line arguments.
- ;
- ; ERROR LEVEL values returned
- ; 0 UNDERLI2 succeeded.
- ; 1 No EGA present.
- ; 2 Usage error.
- ; 3 Not DOS 2.x or DOS 3.x.
- ; 4 IS_RESIDENT found a memory allocation error.
- ; 5 UNDERLI2 tried to unload a resident incarnation,
- ; but IS_RESIDENT couldn't find one.
- ; 6 UNDERLI2 tried to unload a resident incarnation,
- ; but there was another program chained to INT 10H after
- ; the incarnation IS_RESIDENT found.
- ; 7 DOS function 49H (Release memory) failed.
- ;
- ; This program modifies the Enhanced Color Adapter's BIOS regs
- ; to allow underlining to be displayed with the enhanced graphics
- ; adapter and to change selected palette values. Because many `
- ; programs initialize the display prior to using it, any fixes to
- ; the BIOS registers will be reset back to their initial states.
- ; This program will correct the BIOS register problems after each
- ; reset.
- ;
- ; REQUIREMENTS: Microsoft Macro Assembler 4.0
- ; IBM Linker
- ; IBM EXE2BIN
- ; ISRESDNT.OBJ
- ;
- ; COMPILATION: MASM UNDERLI2;
- ; LINK UNDERLI2 ISRESDNT;
- ; EXE2BIN UNDERLI2 UNDERLI2.COM
- ;
- ;
- ; ISRESDNT is a subroutine which I wrote to determine
- ; whether a program is already resident. After it is run:
- ; AX indicates the result of the procedure:
- ; = 0 if it does not find a copy already resident
- ; = 1 if it finds a copy already resident
- ; = -1 if the DOS major version is not legal
- ; = -2 if there is a memory allocation error
- ; CF is set if a copy of this program is resident or if the
- ; DOS version is not legal
- ; DS = DS for the first copy of this program in memory. Note
- ; that if no earlier copy is resident, it is DS of the
- ; calling program.
- ; ES = DS for the calling program.
- ;
- ; I based UNDERLI2.ASM on Gerald S. Kaplan's UNDERLIN.ASM,
- ; which he published in "PC Tech Journal", Vol. 5, No. 9
- ; (September, 1987), p. 49.
-
-
- ; Author : Lew Paper
- ; Date written: 12/15/87
- ; Revisions :
-
- .XLIST
- SUBTTL Switches, Directives, Equates, Macros and Start
- .LIST
- PAGE
- ;-----------------------------------------------------------------------------
- ; SWITCH SETTINGS
- ;-----------------------------------------------------------------------------
-
- resident_int EQU 10H
-
- prototype EQU 0
-
- ;-----------------------------------------------------------------------------
- ; INITIAL DIRECTIVES
- ;-----------------------------------------------------------------------------
-
- EXTRN is_resident:NEAR
-
- ;Standard handles
- StdIn EQU 0 ; Standard input device
- StdOut EQU 1 ; Standard output device
- StdErr EQU 2 ; Standard error device
- StdAux EQU 3 ; Standard auxiliary device
- StdPrn EQU 4 ; Standard printer device
-
- FALSE EQU 0 ; FALSE compare
- TRUE EQU 0FFFFH ; TRUE compare
-
- tab EQU 09h ; ASCII tab
- lf EQU 0Ah ; line feed
- cr EQU 0Dh ; carriage return
- blank EQU 20h ; ASCII blank
-
- cmdtail EQU 80h ; Offset of command tail
-
- doscall MACRO
- INT 21h ; call MS-DOS function
- ENDM ; doscall
-
- ;; DISplay STRing from memory
- dis_str MACRO string ;; display a string
- MOV DX,OFFSET string
- MOV AH,09h
- doscall
- ENDM ; dis_str
-
- ;; Macro to write string to handle. Note that it can change AX,
- ;; BX, CX, DX. It assumes that DS contains the data segment for string.
- ;; It depends on string_length containing the number of bytes in the string.
- write_str MACRO string, handle
- MOV AH,40H
- MOV BX,handle
- MOV CX,string&_length
- LEA DX,string
- doscall
- ENDM ; write_str
-
- ;; String to compare a command line argument to and its length
- underline_action_string MACRO name
- name&_value DB "&name"
- name&_length EQU $ - OFFSET name&_value
- ENDM ; underline_action_string
-
- ;; Check whether the command line argument is "name". If so, set
- ;; underline_action and go on to next argument. Otherwise, fall through
- ;; to end.
- ;; check_underline_action depends on the convention that the string
- ;; of "name" is in name&_string and its length is in name&_length.
- ;; MACRO underline_action_string constructs these variables.
- check_underline_action MACRO name
- LOCAL not_name
- CMP CX,name&_length ;; Is it worth comparing?
- JNZ not_name ;; No
- PUSH CX ;; Length of argument
- PUSH SI ;; Offset of argument
- MOV DI,OFFSET name&_value ;; String to check
- REPZ CMPSB ;; Compare them
- POP SI ;; Restore offset of argument
- POP CX ;; Restore length of argument
- JNZ not_name ;; Not this parameter
- MOV underline_action,name
- JMP SHORT get_parameter_loop ;; Get next parameter
- not_name:
- ENDM ; check_underline_action
-
- ;; Jump to not_a_digit if [BX] is not a digit. Internal to MACRO
- ;; convert_bx_to_integer.
- test_for_digit MACRO not_a_digit
- CMP BYTE PTR [BX],'9'
- JA not_a_digit
- CMP BYTE PTR [BX],'0'
- JB not_a_digit
- ENDM ; test_for_digit
-
- ;; Convert [BX] to an integer in AX. At end, BX points to the next
- ;; character of the argument and CX is the count of characters remaining.
- ;; If the first character of [BX] is not an integer, set carry.
- convert_bx_to_integer MACRO
- LOCAL not_an_integer, exit, convert_loop
-
- CLC ;; Clear carry for no error
- test_for_digit not_an_integer ;; -1 => AX if first character
- ;; is not a digit
- XOR AX,AX ;; 0 => AX
- MOV AL,[BX]
- SUB AX,'0' ;; Convert to digit
- convert_loop:
- INC BX ;; Point at next digit
- DEC CX
- JCXZ exit ;; Argument done
- test_for_digit exit ;; Conversion done inside argument
- MOV DX,AX ;; Multiply number by 10 => DX
- SHL DX,1
- SHL DX,1
- ADD DX,AX
- SHL DX,1
- XOR AX,AX ;; Next digit to AX
- MOV AL,[BX]
- SUB AX,'0'
- ADD AX,DX
- JMP convert_loop
-
- not_an_integer:
- STC
-
- exit:
- ENDM ; convert_bx_to_integer
-
- ;; Change all palette values. Assumes DS is data segment of resident
- ;; incarnation.
- change_palette MACRO
- LOCAL change_single_palettes, change_palette_loop, change_palette_exit
-
- CMP reset_palette,0
- JZ change_single_palettes
- PUSH ES ;; Change all palettes and overscan
- MOV AX,DS
- MOV ES,AX
- MOV AX,1002H ;; BIOS set palette call
- MOV DX,OFFSET all_palettes
- INT 10H
- POP ES ;; Restore register
- JMP change_palette_exit
-
- change_single_palettes:
- MOV CX,palette_value_count
- JCXZ change_palette_exit
- MOV SI,OFFSET palette_value
- change_palette_loop:
- MOV AX,1000H ;; BIOS set palette call
- MOV BX,[SI]
- INT 10H
- INC SI
- INC SI
- LOOP change_palette_loop
-
- change_palette_exit:
- ENDM ; change_palette
-
- ;; Set underlining register. Assumes DS is data segment of resident
- ;; incarnation.
- set_underlining MACRO
- PUSH DS
- MOV AX,40H ;; Set up addressibility of BIOS data
- MOV DS,AX
- MOV DX,DS:63H ;; CRTC base address
- MOV AL,014H ;; Register 14 is underline register
- OUT DX,AL ;; Indicate change to register 14
- INC DX ;; Now point to CRTC data register
- POP DS ;; Segment of resident incarnation
- MOV AL,scanline
- OUT DX,AL ;; Send it to register 14
- ENDM ;; set_underlining
-
- ; Values for scanline
- DEFAULT_ON_LINE_NUMBER EQU 13
- OFF_LINE_NUMBER EQU 14
-
- ; Values for underline_action
- NONE EQU 0
- ON EQU 1
- OFF EQU 2
- SWITCH EQU 3
- KEEP EQU 4
- UNLOAD EQU 5
- NUMBER EQU 6
-
- COMSEG SEGMENT PARA PUBLIC 'CODE'
- ASSUME CS:COMSEG,DS:COMSEG,ES:COMSEG,SS:COMSEG
-
- ORG 0
- seg_org EQU $ ; Start of loaded program
-
- ORG 2CH
- env_adr LABEL WORD ; offset of environment in PSP
-
- ORG 100H
-
- main PROC FAR
- start:
- JMP booster ; Set up portion
-
- .XLIST
- SUBTTL Resident Part of Program
- .LIST
- PAGE
- ;-----------------------------------------------------------------------------
- ; DATA AREAS
- ;-----------------------------------------------------------------------------
-
- old_interrupt1 DD ? ; Original branch for calling interrupt
-
- on_line_number DB DEFAULT_ON_LINE_NUMBER
- scanline DB OFF_LINE_NUMBER
- palette_value DW 16 DUP (?) ; High word is value to set
- ; Low word is palette register to set
- palette_value_count DW 0
-
- all_palettes DB 17 DUP (?) ; 16 palette register values and
- ; overscan register value for border
- reset_palette DB 0 ; 0 means don't reset palette
- palette_data_length EQU $ - OFFSET palette_value
-
- signature DW (('U' SHL 8) OR 'N') OR 8080H
- test_string DW 0
- DB 'UNDERLI2'
- test_string_length EQU $ - OFFSET test_string
-
- ;-----------------------------------------------------------------------------
-
- entry:
- AND AH,AH ; Must be interrupt 10H, is it
- ; set mode?
- JZ set_mode ; Yes
- JMP CS:old_interrupt1 ; Go to BIOS and do not return
-
- set_mode:
- PUSHF ; Simulate interrupt
- CALL CS:old_interrupt1 ; Perform the called interrupt
- PUSH DS ; Minimal save registers
- PUSH AX
- MOV AX,CS ; Establish DS
- MOV DS,AX
-
- set_underlining
- change_palette
-
- interrupt_exit:
- POP AX ; Restore minimally saved registers
- POP DS
- empty_iret:
- IRET ; Invoked by an interrupt
- main ENDP
-
- lst_byt: ; last byte to save
-
- resident_length EQU (OFFSET lst_byt - seg_org + 15) shr 4
- ; Number of paragraphs to save
-
-
- .XLIST
- SUBTTL Transient Part of Program (Booster)
- .LIST
- PAGE
- ;-----------------------------------------------------------------------------
- ; SUBROUTINES
- ;-----------------------------------------------------------------------------
-
- ; I modified these two procedures from "PC Magazine", Vol 6, No. 22
- ; (December 22, 1987), pp 366-7, for a COM program. Ray Duncan wrote
- ; them. Note that they do not support quoted arguments
-
- ; ARGC.ASM: return count of command line arguments.
- ; Treats blanks and tabs as whitespace, carriage
- ; returns as terminator
- ;
- ; (C) 1987 Ziff Communications co.
- ;
- ; Returns: AX = argument count (always >= 1)
- ; Other registers preserved
- ;
-
- argc PROC NEAR
-
- PUSH BX ; Save original BX
- PUSH CX
- MOV AX,1 ; Force original count >= 1
- MOV BX,cmdtail ; Beginning of command line
-
- argc1: MOV CX,-1 ; Set flag = outside argument
-
- argc2: INC BX ; Point to next character
- CMP BYTE PTR [BX],cr
- JE argc3 ; Exit if carriage return
- CMP BYTE PTR [BX],blank
- JE argc1 ; Outside argument if ASCII blank
- CMP BYTE PTR [BX],tab
- JE argc1 ; Outside argument if ASCII tab
-
- JCXZ argc2 ; Jump if already inside argument
-
- INC AX ; Else found argument, count it
- NOT CX ; Set flag inside argument
- JMP argc2
-
- argc3: POP CX ; Restore original BX and CX
- POP BX
- ret
-
- argc ENDP
-
- ;
- ; ARGV.ASM Return address and length of specified
- ; command line argument or fully qualified program
- ; name. Treats blanks and tabs as whitespace, cariage
- ; returns as terminator.
- ;
- ; (C) 1987 Ziff Communications Co.
- ;
- ; Call with: AX = argument number (0 based)
- ;
- ; Returns: BX = argument offset
- ; AX = argument length
- ; (0=argument not found)
- ; ES = segment of environment block
- ; if argv[0] (see below)
- ; Other registers preserved.
- ;
- ; If called with AX=0 a(argv[0]) and running under
- ; MS-DOS version 3.0 or later, returns ES:BX pointing
- ; to program name in environment block and AX= length,
- ; otherwise returns ES:BX UNCHANGED AND AX=0.
- ;
-
- argv PROC NEAR ; Get address and length of
- ; command tail argument
-
- PUSH CX ; Save original CX and DI
- PUSH DI
-
- OR AX,AX ; Is it argument 0?
- JZ argv8 ; Yes, jump to get program name
-
- MOV BX,cmdtail ; Beginning of command line
- XOR AH,AH ; Initialize argument counter
-
- argv1: MOV CX,-1 ; Set flag = outside argument
-
- argv2: INC BX ; Point to next character
- CMP BYTE PTR [BX],cr
- JE argv7 ; Exit if carriage return
- CMP BYTE PTR [BX],blank
- JE argv1 ; Ouside argument if ASCII blank
- CMP BYTE PTR [BX],tab
- JE argv1 ; Ouside argument if ASCII tab
-
- ; if not blank or tab...
- JCXZ argv2 ; Jump if already inside argument
- INC AH ; Else count arguments found
- CMP AH,AL ; Is this the one we're looking for?
- JE argv4 ; Yes, go find its length
- NOT CX ; No, set flag = iside argument
- JMP argv2 ; and look at next character
-
- argv4: ; Found desired argument, now
- ; determine its length...
- MOV AX,BX ; Save param, starting address
-
- argv5: INC BX ; Point to next character
- CMP BYTE PTR [BX],cr
- JE argv6 ; Found if carriage return
- CMP BYTE PTR [BX],blank
- JE argv6 ; Found if ASCII blank
- CMP BYTE PTR [BX],tab
- JNE argv5 ; Found if ASCII tab
-
- argv6: XCHG BX,AX ; Set BX = argument offset
- SUB AX,BX ; And AX = argument length
- JMP SHORT argvx ; Return to caller
-
- argv7: XOR AX,AX ; Set AX = 0, argument not found
- JMP SHORT argvx ; Return to caller
-
- argv8: ; Special handling for argv=0
- MOV AX,3000H ; Check if DOS 3.0 or later
- doscall ; (Force AL=0 in case DOS=1)
- CMP AL,3
- JB argv7 ; DOS 1 or 2, return null param
- MOV ES,[env_adr] ; Get environment segment from PSP
- XOR DI,DI ; Find program name by
- XOR AL,AL ; first skipping over all the
- MOV CX,-1 ; environment variables
- CLD
- argv9: REPNE SCASB ; Scan for double null (can't use
- SCASB ; SCASW since might be odd addr.)
- JNE argv9 ; Loop if it was a single null
- ADD DI,2 ; Skip count word in environment
- MOV BX,DI ; Save program name address
- MOV CX,-1 ; Now find its length
- REPNE SCASB ; Scan for another null byte
- NOT CX ; Convert CX to length
- DEC CX
- MOV AX,CX ; Return length in AX
-
- argvx: ; Common exit point
- POP DI ; Restore original CX and DI
- POP CX
- RET
-
- argv ENDP
-
- ; UPPER_CASE_COMMAND_LINE:
- ; Set the original command line to upper case.
- ;
- ; (C) 1987 Lew Paper
- ;
- ; Returns: Nothing
- ; All registers preserved
- ;
-
- upper_case_command_line PROC NEAR
-
- PUSH AX ; Save original AX and BX
- PUSH BX
- MOV BX,cmdtail ; Beginning of command line
-
- upper_case_command_line_1:
- INC BX ; Point to next character
- CMP BYTE PTR [BX],'a'
- JB upper_case_command_line_2
- ; Check for carriage return
- CMP BYTE PTR [BX],'z'
- JA upper_case_command_line_1
- AND BYTE PTR [BX],05FH ; Convert to upper case
- JMP upper_case_command_line_1
-
- upper_case_command_line_2:
- CMP BYTE PTR [BX],cr ; Check for end of line
- JNE upper_case_command_line_1
-
- POP BX ; Restore original AX and BX
- POP AX
- ret
-
- upper_case_command_line ENDP
-
- IF prototype NE 0
-
- ; BYTE_TO_DEC_99 - binary to ASCII decimal, 2 places
-
- ; Call with AL = value to convert
- ; DI = address for string
-
- ; Stores leading zeros
-
- ; Dan Daetwyler's binary to ASCII decimal conversion routines.
- ; Modified by Lew Paper to take advantage of word storing
-
- byte_to_dec_99 PROC NEAR
- CMP AL,9 ;One digit?
- JG byte_to_dec_2_digit ;No
- MOV AH,' ' ;Leading space
- OR AL,'0' ;Make one digit ASCII
- JMP SHORT byte_to_dec_save
-
- byte_to_dec_2_digit:
- AAM ;Number / 10 => AH
- ;Number mod 10 => AL
- OR AX,'00' ;make them ASCII
- byte_to_dec_save:
- XCHG AH,AL ;Number mod 10 => AH
- ;Number / 10 => AL
- STOSW ;Stores as AL, AH. LP
- RET ;back to caller
- byte_to_dec_99 ENDP
-
- ENDIF ; IF prototype NE 0
-
- ;-----------------------------------------------------------------------------
- ; DATA FOR BOOSTER
- ;-----------------------------------------------------------------------------
-
- ; Opening message for StdOut
- opening_msg DB cr, lf, 'UNDERLI2, modified by Lew Paper', cr, lf
- DB 'from UNDERLIN: By Gerald S. Kaplan', cr, lf, lf, '$'
-
- ; Result messages for StdOut
-
- installed_msg DB 'Installed UNDERLI2 in memory', cr, lf, lf, '$'
-
- modified_msg DB 'Modified existing UNDERLI2 in memory', cr, lf, lf, '$'
-
- unloaded_msg DB 'Removed UNDERLI2 from memory', cr, lf, lf, '$'
-
- ; Error messages for StdErr
-
- no_EGA_msg DB "You don't need UNDERLI2 because you don't "
- DB 'have an installed EGA.'
- DB cr, lf, lf
- no_EGA_msg_length EQU $ - OFFSET no_EGA_msg
-
- usage DB 'Usage', cr, lf
- DB ' underli2 [on|off|switch|keep|unload|#] '
- DB '[/s ] [/p<k1>=<n1>] [/p<k2>= ...', cr, lf
- DB ' where', cr, lf
- DB ' "on" turns underlining on.', cr, lf
- DB ' "off" turns underline off.', cr, lf
- DB ' "switch" reverses the underlining setting.'
- DB cr, lf
- DB ' "keep" keeps the underlining setting.'
- DB cr, lf
- DB ' "unload" removes underli2 from memory.'
- DB cr, lf
- DB ' # turns on underlining at scan line #.'
- DB cr,lf
- DB " If you don't specify one of these "
- DB 'values,', cr, lf
- DB ' underli2 reverses the underlining setting.'
- DB cr, lf
- DB ' "/s" resets all unspecified palettes '
- DB 'to their', cr, lf
- DB ' standard values.', cr, lf
- DB ' "/p<ki>=<ni>" sets palette ki '
- DB '(maximum 15)', cr, lf
- DB ' to value ni (maximum 63 = 03FH). Enter '
- DB 'ki and ni', cr, lf
- DB ' as decimal numbers.'
- DB cr, lf, lf
- usage_length EQU $ - OFFSET usage
-
- wrong_DOS_msg DB 'UNDERLI2 requires DOS 2 or DOS 3'
- DB cr, lf, lf
- wrong_DOS_msg_length EQU $ - OFFSET wrong_DOS_msg
-
- memory_alloc_error_msg DB 'IS_RESIDENT in UNDERLI2 '
- DB 'found a memory allocation error'
- DB cr, lf, lf
- memory_alloc_error_msg_length EQU $ - OFFSET memory_alloc_error_msg
-
- not_resident_error_msg DB "UNDERLI2 isn't resident, "
- DB 'so there is nothing to UNLOAD'
- DB cr, lf, lf
- not_resident_error_msg_length EQU $ - OFFSET not_resident_error_msg
-
- not_end_of_chain_msg DB "You can't UNLOAD UNDERLI2 because INT 10H jumps "
- DB 'to another program first'
- DB cr, lf, lf
- not_end_of_chain_msg_length EQU $ - OFFSET not_end_of_chain_msg
-
- argument_count DW 0
- palette_value_flag DB 16 DUP (0)
- standard_palette_values DB 00H ; High word is value to set
- ; Low word is palette register to set
- DB 01H, 02H, 03H
- DB 04H, 05H, 06H, 07H
- DB 38H, 39H, 3AH, 3BH
- DB 3CH, 3DH, 3EH, 3FH
- DB 0 ; Overscan register
- exitval DB 0 ; Exit value
- is_resident_value DB 0FFH ; 0 if not resident, 1 if resident
- old_UNDERLI2_segment DW (?)
-
- ; Parameter values for underline_action
- underline_action_string ON
- underline_action_string OFF
- underline_action_string SWITCH
- underline_action_string KEEP
- underline_action_string UNLOAD
-
- underline_action DB NONE
-
- fail49 DB cr, lf, "DOS function 49H error", cr, lf
- DB "Failed to free environment block", cr, lf, cr, lf
- fail49_length EQU $ - OFFSET fail49
-
- IF prototype EQ 1
- param_list DB 'underline_action = '
- ula DW (?)
- DB cr, lf, 'on_line_number = '
- oln DW (?)
- DB cr, lf, 'scanline = '
- sl DW (?)
- DB cr, lf, 'CHANGED PALETTE VALUES'
- DB cr, lf, 'Palette'
- DB cr, lf, ' Number Value$'
- pl DB cr, lf, ' '
- pln DW (?)
- DB ' '
- plv DW (?)
- DB '$'
- crlf2 db cr, lf, cr, lf, '$'
- ENDIF ; IF prototype EQ 1
- ;-----------------------------------------------------------------------------
-
- booster PROC NEAR ; Set up resident program
-
- dis_str opening_msg
- MOV BX,DS ; Check for EGA with the method from
- ; Robert Jourdain, "PROGRAMMER'S
- ; PROBLEM SOLVER for the IBM PC, XT
- ; and AT" (New York, Brady
- ; Communications Company Inc., 1986),
- ; p. 9.
- ; Save DS
- MOV AX,40H ; Segment for BIOS data area
- MOV DS,AX
- MOV AL,[87H] ; 487H is 0 if no EGA is present
- MOV DS,BX ; Restore DS
- AND AL,AL ; Is EGA present?
- JNZ EGA_present
- write_str no_EGA_msg, StdErr
- MOV AL,1
- JMP exit_loc
-
- EGA_present:
- CALL argc
- CMP AX,1
- JG read_command_line
- MOV underline_action,SWITCH
- JMP check_residence
-
- read_command_line:
- CALL upper_case_command_line
- MOV argument_count,AX
- MOV AX,1
-
- get_parameter:
- PUSH AX
- CALL argv
- MOV CX,AX ; Length of argument
- CMP BYTE PTR [BX],'/' ; Check for palette value
- JZ check_argument_type
- CMP BYTE PTR [BX],'-'
- JZ check_argument_type
- CMP underline_action,NONE ; Are two actions specified?
- JZ set_underline_action_1
- JMP usage_exit
-
- set_underline_action_1: ; Avoid relative jump out of range
- JMP set_underline_action
-
- check_argument_type:
- INC BX
- DEC CX
- JCXZ usage_error_1
- CMP BYTE PTR [BX],'S'
- JE check_reset_palette_request
- CMP BYTE PTR [BX],'P'
- JNE usage_error_1
- INC BX ; Must have palette register number
- DEC CX
- JCXZ usage_error_1
- JMP SHORT get_palette_number
-
- check_reset_palette_request:
- CMP reset_palette,0 ; Has "/s" already been specified?
- JNZ usage_error_1 ; Yes
- DEC CX ; Must be end of argument
- JCXZ set_reset_palette
-
- usage_error_1: ; Avoid relative jump out of range
- JMP usage_exit
-
- set_reset_palette:
- MOV reset_palette,1
- JMP get_parameter_loop
-
- get_palette_number:
- convert_bx_to_integer ; Palette number
- JC usage_error_1
- CMP AX,15
- JA usage_error_1
- MOV SI,AX
- CMP palette_value_flag[SI],0
- ; Has it already been set?
- JNE usage_error_1
- ; Yes
- MOV palette_value_flag[SI],1
- ; Set to avoid duplicates
- MOV SI,palette_value_count
- ; Number of next open word in
- ; palette_value
- SHL SI,1 ; Convert to word index
- MOV palette_value[SI],AX ; Palette register to be set
- JCXZ palette_value_in_next_arg
- INC BX ; Bypass filler character
- DEC CX
- JCXZ set_palette_value_error
- get_palette_value:
- convert_bx_to_integer
- JC set_palette_value_error
- JCXZ check_palette_value ; Must be end of argument
- JMP SHORT set_palette_value_error
-
- palette_value_in_next_arg:
- POP AX
- INC AX
- CMP AX,argument_count
- JGE set_palette_value_error
- ; No next argument
- PUSH AX
- CALL argv
- MOV CX,AX
- JMP get_palette_value
-
- check_palette_value:
- CMP AX,03FH ; Must be less than 64
- JA set_palette_value_error
- XCHG AL,AH ; palette_value => AH
- ; 0 => AL
- OR palette_value[SI],AX
- ; Save palette value
- INC palette_value_count
- JMP get_parameter_loop
-
- set_palette_value_error: ; Avoid relative jump out of range
- JMP usage_exit
-
- set_underline_action:
- MOV SI,BX ; Offset of argument
- convert_bx_to_integer
- JC underline_actions
- JCXZ reset_scanline
- JMP usage_exit
-
- reset_scanline:
- MOV on_line_number,AL
- MOV underline_action,NUMBER
- JMP SHORT get_parameter_loop
-
- underline_actions:
- check_underline_action ON
- check_underline_action OFF
- check_underline_action SWITCH
- check_underline_action KEEP
- check_underline_action UNLOAD
- JMP usage_exit
-
- get_parameter_loop:
- POP AX
- INC AX
- CMP AX,argument_count
- JGE check_reset_palette
- JMP get_parameter
-
- check_reset_palette:
- MOV AL,reset_palette
- AND AL,AL ; Reset unspecified palette registers?
- JZ check_residence ; No
- MOV CX,palette_value_count
- ; Any palette value registers
- ; specified?
- JCXZ set_all_palettes ; NO
- MOV SI,OFFSET palette_value
- XOR BH,BH ; BX will index the changes
- ; in standard_palette_values
- change_std_palette_values:
- LODSW ; Changed palette value => AX
- ; Point SI at next changed
- ; palette value
- MOV BL,AL
- MOV standard_palette_values[BX],AH
- LOOP change_std_palette_values
-
- set_all_palettes:
- MOV SI,OFFSET standard_palette_values
- MOV DI,OFFSET all_palettes
- MOV CX,17
- REP MOVSB
-
- check_residence:
- IF prototype EQ 1
- MOV DI,OFFSET ula
- MOV AL,underline_action
- CALL byte_to_dec_99
- MOV DI,OFFSET oln
- MOV AL,on_line_number
- CALL byte_to_dec_99
- MOV DI,OFFSET sl
- MOV AL,scanline
- CALL byte_to_dec_99
- dis_str param_list
- CMP reset_palette,0
- JZ not_reset_1
- MOV CX,17
- MOV SI,OFFSET all_palettes
- pv_reset_loop:
- MOV AX,SI
- SUB AX,OFFSET all_palettes
- MOV DI,OFFSET pln
- CALL byte_to_dec_99
- XOR AH,AH
- LODSB
- MOV DI,OFFSET plv
- CALL byte_to_dec_99
- dis_str pl
- LOOP pv_reset_loop
- JMP SHORT after_pv
-
- not_reset_1:
- MOV CX,palette_value_count
- JCXZ after_pv
- MOV SI,OFFSET palette_value
- pv_loop:
- MOV AX,[SI]
- XOR AH,AH
- MOV DI,OFFSET pln
- CALL byte_to_dec_99
- LODSW
- XCHG AL,AH
- XOR AH,AH
- MOV DI,OFFSET plv
- CALL byte_to_dec_99
- dis_str pl
- LOOP pv_loop
- after_pv:
- dis_str crlf2
- ELSE ; prototype EQ 0
- MOV SI,OFFSET signature ; Set up for is_resident
- MOV DI,OFFSET test_string
- MOV AX,test_string_length
- CALL is_resident
- CMP AX,-1 ; Was there an error?
- JG check_UNLOAD ; No
- MOV BX,ES ; Restore DS
- MOV DS,BX
- JZ wrong_DOS
- write_str memory_alloc_error_msg, StdErr
- MOV AL,4
- JMP exit_loc
-
- wrong_DOS:
- write_str wrong_DOS_msg, StdErr
- MOV AL,3
- JMP exit_loc
-
- check_UNLOAD:
- CMP ES:underline_action,UNLOAD
- JZ anything_to_UNLOAD
- JMP not_UNLOAD
-
- anything_to_UNLOAD:
- OR AX,AX ; Is a copy of UNDERLI2 resident?
- JNZ check_end_of_chain ; Yes
- write_str not_resident_error_msg, StdErr
- MOV AL,5
- JMP exit_loc
-
- check_end_of_chain:
- MOV ES:old_UNDERLI2_segment,DS
- MOV AX,ES ; Set DS to this incarnation
- MOV DS,AX
- MOV AX,3500H OR resident_int
- ; Get interrupt vector
- doscall
- MOV AX,ES ; Segment of interrupt vector
- CMP AX,old_UNDERLI2_segment
- JNZ not_end_of_chain
- CMP BX,OFFSET entry ; Offset of interrupt vector
- JZ end_of_chain
- not_end_of_chain:
- write_str not_end_of_chain_msg, StdErr
- MOV AL,6
- JMP exit_loc
-
- end_of_chain:
- MOV AH,49H ; Prepare to release memory
- MOV ES,old_UNDERLI2_segment
- MOV CX,DS ; Save this segment
- LDS DX,ES:old_interrupt1 ; To restore interrupt if
- ; release memory works
- doscall ; Now release memory
- JNC release_memory_worked
- MOV DS,CX ; Restore segment
- write_str fail49, StdErr
- MOV AL,7
- JMP exit_loc
-
- release_memory_worked:
- MOV AX,2500H OR resident_int
- ; Restore old interrupt
- CLI
- doscall
- STI
- MOV DS,CX ; Restore segment
- dis_str unloaded_msg
- JMP set_error_level
-
- not_UNLOAD:
- MOV ES:is_resident_value,AL
- ; ES is segment for this incarnation
- CMP ES:underline_action,ON
- ; Now set scanline
- JNZ not_ON
- set_scanline_ON:
- MOV AL,on_line_number ; Resident incarnation
- MOV scanline,AL
- JMP SHORT scanline_set
-
- not_ON:
- CMP ES:underline_action,OFF
- JNZ not_OFF
- set_scanline_OFF:
- MOV scanline,OFF_LINE_NUMBER
- JMP SHORT scanline_set
-
- not_OFF:
- CMP ES:underline_action,SWITCH
- JNZ not_SWITCH
- CMP scanline,OFF_LINE_NUMBER
- JZ set_scanline_ON
- JMP SHORT set_scanline_OFF
-
- not_SWITCH:
- CMP ES:underline_action,NUMBER
- JNZ scanline_set ; Must be keep
- MOV AL,ES:on_line_number ; Move new line number to
- ; resident incarnation. It is
- ; cheaper to move to itself than
- ; to test and branch
- MOV on_line_number,AL
- JMP SHORT set_scanline_ON
-
- scanline_set:
- TEST ES:is_resident_value,0FFH
- ; Is UNDERLIN2 already resident?
- JZ install ; No
- MOV BX,DS ; Move all palette data to
- ; installed incarnation
- ; Installed incarnation segment => ES
- ; This incarnation segment => DS
- MOV DX,ES
- MOV DS,DX
- MOV ES,BX
- MOV SI,OFFSET palette_value
- MOV DI,OFFSET palette_value
- MOV CX,palette_data_length
- REP MOVSB
- MOV DS,BX ; Restore segments
- ; Installed incarnation segment => DS
- ; This incarnation segment => ES
- MOV ES,DX
- JMP SHORT run_from_command_line
-
- install:
- ; Free memory allocated for environment. If DOS can not do it, return
- ; without installing program and with error code 6.
- MOV ES,env_adr ; Get address of environment
- MOV AH,49H ; Free allocated memory
- doscall ; Call MS-DOS
- JNC setvect ; Branch if no error
- write_str fail49, StdErr ; Inform that there was an error
- MOV AL,7
- JMP exit_loc
-
- setvect: ; Environment removed
-
- ; Save old interrupt
- MOV AH,35H ; Get interrupt vector
- MOV AL,resident_int ; Interrupt number
- doscall
- MOV WORD PTR old_interrupt1,BX
- ; Offset of interrupt vector
- MOV WORD PTR old_interrupt1[2],ES
- ; Segment of interrupt vector
- MOV AX,CS ; Reestablish ES
- MOV ES,AX
- OR BX,WORD PTR old_interrupt1[2]
- ; Were both segment and offset zero?
- JNZ set_new_interrupt ; No
- MOV WORD PTR old_interrupt1,OFFSET empty_iret
- ; Point to just an IRET
- MOV WORD PTR old_interrupt1[2],CS
-
- set_new_interrupt:
- MOV DX,OFFSET entry ; Entry point for interrupt
- MOV AL,resident_int ; Interrupt number to reset
- MOV AH,25H ; Set interrupt number
- CLI ; Disable interrupts
- doscall
- STI ; Enable interrupts
-
- run_from_command_line:
- change_palette
- CMP underline_action,KEEP
- JZ booster_exit
- set_underlining
-
- booster_exit:
- TEST ES:is_resident_value,0FFH
- ; Did you install this time?
- JNZ display_modified_msg ; No
-
- ; Terminate and stay resident
- dis_str installed_msg
- MOV DX,resident_length ; Number of paragraphs to save
- MOV AX,3100H ; Terminate process and remain
- ; resident. Return code = 0.
- doscall ; Call MS-DOS
-
- display_modified_msg:
- MOV AX,ES ; Restore DS to this incarnation
- MOV DS,AX
- dis_str modified_msg
-
- ENDIF ; IF prototype EQ 1
-
- set_error_level:
- MOV AL,exitval ; Set error level
- JMP SHORT exit_loc
-
- usage_exit:
- write_str usage,StdErr
- MOV AL,2
-
- exit_loc: MOV AH,4CH ; Terminate process function number
- doscall ; Return to DOS
-
- booster ENDP
-
- ;-----------------------------------------------------------------------------
- ; OVERALL END
- ;-----------------------------------------------------------------------------
- COMSEG ENDS
- END start
-
-